home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Amiga Format CD 44
/
Amiga Format CD44 (1999-08-26)(Future Publishing)(GB)(Track 1 of 3)[!][issue 1999-10].iso
/
-in_the_mag-
/
workbench
/
pcmser
/
source
/
pcmser.device.s
< prev
next >
Wrap
Text File
|
1999-07-28
|
30KB
|
1,287 lines
incdir include/
include exec/exec.i
include exec/exec_lib.i
include dos/dos_lib.i
include devices/serial.i
include resources/card.i
include resources/cardres_lib.i
incdir
include modem/macros.i
include modem/uart.i
include modem/cistpl.i
include modem/pcmser.i
;--Constants
REVISION=6
VERSION=0
MYPRI=0
UNITS=1
section main,code
;------------------------------------------------------------------------
j moveq #0,d0 ;Stupid user tried to start us!
rts
initddescript dc.w RTC_MATCHWORD ;RT_MATCHWORD
dc.l initddescript ;RT_MATCHTAG
dc.l endofcode ;RT_ENDSKIP
dc.b RTF_AUTOINIT ;RT_FLAGS
dc.b VERSION ;RT_VERSION
dc.b NT_DEVICE ;RT_TYPE
dc.b MYPRI ;RT_PRI
dc.l myname
dc.l idstring
dc.l init
myname dc.b "pcmser.device",0
dc.b "$VER: "
idstring dc.b "pcmser.device 0.6 (24.08.97)",13,10,0
cnop 0,4
init dc.l MYDEV_SIZEOF
dc.l functable
dc.l datatable
dc.l initroutine
;--Function table
functable dc.l opendevice ;open -6
dc.l closedevice ;close -12
dc.l expunge ;expunge -18
dc.l resvec ;reserved -24
dc.l beginio ;BeginIO -30
dc.l abortio ;AbortIO -36
dc.l -1 ;marks end of list
;---Data table
datatable dc.l 0
dc.l 0
dc.b NT_DEVICE
dc.b 0
dc.l myname
dc.b LIBF_SUMUSED!LIBF_CHANGED ;UBYTE LIB_FLAGS
dc.b 0 ;UBYTE LIB_pad
dc.w 0 ;UWORD LIB_NEGSIZE
dc.w 0 ;UWORD LIB_POSSIZE
dc.w VERSION ;UWORD LIB_VERSION
dc.w REVISION ;UWORD LIB_REVISION
dc.l idstring ;APTR LIB_IDSTRING
dc.l 0 ;ULONG LIB_SUM
dc.w 0 ;UWORD LIB_OPENCNT
_SysBase dc.l 0
devicebase dc.l 0
;========================================================================
;---initroutine---
;d0=devicebase
;a0=seglist
;
;return d0
;devicebase=ok
;0=error
;========================================================================
initroutine movem.l d1-a6,-(sp)
move.l d0,a5
move.w #VERSION,LIB_VERSION(a5)
move.w #REVISION,LIB_REVISION(a5)
move.l d0,devicebase
move.l a0,MD_SEGLIST(a5)
move.l 4.w,_SysBase
bsr.w setupdevice
tst.l d0
beq.b .ok
moveq #0,d0
bra.b .end
.ok move.l a5,d0
.end movem.l (sp)+,d1-a6
rts
;========================================================================
;---opendevice--- guaranteed to be single threaded
;d0=unit
;d1=flags
;a1=io-request
;a6=devicebase
;
;return IO_ERROR
;0=ok
;!0=errorcode
;========================================================================
opendevice move.l a6,-(sp)
cmp.l #UNITS,d0
bge.w .error
clr.b IO_ERROR(a1)
mulu #PCMNODE_SIZEOF,d0
add.l #serdata,d0
move.l d0,IO_UNIT(a1)
move.l d0,a0 ;a0=serunit
tst.w PCM_UNITOPENCNT(a0) ;fix the shared access stuff
bne.b .not1st
movem.l a0-a1,-(sp) ;this is the 1st time the
sub.l a1,a1 ;device opened
GET SysBase
CALL FindTask ;get the owner of the device
movem.l (sp)+,a0-a1
move.l d0,PCM_OWNERTASK(a0)
bclr #STATUSB_SHARED,PCM_FLAGS(a0)
btst #SERB_SHARED,IO_SERFLAGS(a1) ;use shared access?
beq.b .sharedcont ;no!
bset #STATUSB_SHARED,PCM_FLAGS(a0) ;yes!
bra.b .sharedcont
.not1st GET SysBase
movem.l a0/a1,-(sp)
sub.l a1,a1
CALL FindTask
movem.l (sp)+,a0/a1
cmp.l PCM_OWNERTASK(a0),d0
beq.b .no7wire ;no need to check CTS/RTS again
btst #STATUSB_SHARED,PCM_FLAGS(a0)
beq.b .sharederr
btst #SERB_SHARED,IO_SERFLAGS(a1) ;shared?
bne.b .no7wire
.sharederr move.b #SerErr_DevBusy,IO_ERROR(a1)
bra.w .end
.sharedcont btst #SERB_7WIRE,IO_SERFLAGS(a1) ;CTS/RTS?
beq.b .no7wire
bset #STATUSB_USE7WIRE,PCM_FLAGS(a0)
move.l PCM_BASEADR(a0),a6
move.b UART_MSR(a6),d0
btst #4,d0
beq.b .no7wire
bset #STATUSB_CTS,PCM_FLAGS(a0)
.no7wire move.l devicebase(pc),a6
addq.w #1,LIB_OPENCNT(a6)
addq.w #1,PCM_UNITOPENCNT(a0)
bclr #LIBB_DELEXP,MD_FLAGS(a6)
move.l #9600,IO_BAUD(a1) ;fill in & set defult settings
move.b #8,IO_READLEN(a1)
move.b #8,IO_WRITELEN(a1)
move.b #1,IO_STOPBITS(a1)
move.l a0,-(sp)
bsr.w setparams
move.l (sp)+,a0
move.l PCM_BASEADR(a0),a1
move.b #0,UART_FCR(a1) ;FIFOs off
btst #STATUSB_USEFIFO,PCM_FLAGS(a0)
beq.b .nofifo
move.b #7,UART_FCR(a1) ;FIFOs on (yeah!!)
.nofifo move.b UART_MSR(a1),d0 ;clear MSR
move.b UART_RBR(a1),d0
move.b UART_LSR(a1),d0
move.b UART_IIR(a1),d0
move.b #%1011,UART_MCR(a1) ;DTR/RTS/master int on
move.b #%1111,UART_IER(a1) ;enable all ints
cmp.w #1,PCM_UNITOPENCNT(a0)
bne.b .notfirstopen
;If this is the first time this unit is opened we need
;to wait a little while to allow the modem to init itself
;otherwise DSR wont come on and some programs will complain.
lea dosname(pc),a1
moveq #37,d0
GET SysBase
CALL OpenLibrary
move.l d0,a6
beq.b .notfirstopen
move.l #30,d1
CALL Delay
move.l a6,a1
GET SysBase
CALL CloseLibrary
.notfirstopen move.l devicebase(pc),a0
bra.b .end
.error move.b #IOERR_OPENFAIL,IO_ERROR(a1)
.end move.l (sp)+,a6
rts
dosname dc.b "dos.library",0
;========================================================================
;---closedevice--- guaranteed to be single threaded
;a6=devicebase
;a1=io-request
;
;return d0
;0=do nothing
;seglist=unload device
;========================================================================
closedevice move.l IO_UNIT(a1),a0
move.l #-1,IO_UNIT(a1)
move.l #-1,IO_DEVICE(a1)
clr.l d0
subq.w #1,LIB_OPENCNT(a6)
subq.w #1,PCM_UNITOPENCNT(a0) ;last opener closed us?
bne.b .end
move.l PCM_BASEADR(a0),a0 ;in that case turn
move.b #0,UART_MCR(a0) ;master int off
move.b #0,UART_IER(a0) ;ints off
btst #LIBB_DELEXP,MD_FLAGS(a6) ;delayed expunge?
bne.b .doexp
btst #DEVINFOB_CONFIGURED,MD_MYFLAGS(a6) ;user removed card?
bne.b .end
.doexp bsr.b expunge ;then expunge
.end rts
;========================================================================
;---expunge--- guaranteed to be single threaded
;a6=devicebase
;
;return d0
;0=do nothing
;seglist=unload device
;========================================================================
expunge movem.l d2/a5-a6,-(sp)
tst.w LIB_OPENCNT(a6)
beq.b .remove
bset #LIBB_DELEXP,MD_FLAGS(a6) ;opencnt was not 0
clr.l d0 ;do delayed expunge
bra.b .end
.remove move.l a6,a5
bsr.w cleanupdevice
move.l MD_SEGLIST(a5),d2
move.l a5,a1
REMOVE
move.l a5,a1
moveq #0,d0
move.w LIB_NEGSIZE(a5),d0
suba.l d0,a1
add.w LIB_POSSIZE(a5),d0
GET SysBase
CALL FreeMem
move.l d2,d0
; COLTESTR ;!!!!!!!!!!!!!!!
.end movem.l (sp)+,d2/a5-a6
rts
;========================================================================
;---beginio---
;a6=devicebase
;a1=iorequest
;========================================================================
beginio movem.l a6,-(sp)
clr.b IO_ERROR(a1)
move.b #NT_MESSAGE,LN_TYPE(a1)
.noread btst #DEVINFOB_CONFIGURED,MD_MYFLAGS(a6)
beq.b .nocard ;card is not configured (removed)
clr.l d0
move.w IO_COMMAND(a1),d0
cmp.l #SER_DEVFINISH+1,d0 ;Is IO_COMMAND to high?
bge.b .unknowncmd
add.w d0,d0
lea .cmdtable(pc),a0
add.w d0,d0
move.l (a0,d0.w),a0
cmp.l #0,a0 ;Unsupported command?
beq.b .unknowncmd
jsr (a0) ;Jump to CMD-code
bra.b .cont
.unknowncmd move.b #IOERR_NOCMD,IO_ERROR(a1)
clr.b IO_FLAGS(a1)
GET SysBase
CALL ReplyMsg
bra.b .cont
.nocard cmp.w #CMD_READ,IO_COMMAND(a1)
beq.b .nocardreadreq
move.b #IOERR_SELFTEST,IO_ERROR(a1)
clr.b IO_FLAGS(a1)
GET SysBase
CALL ReplyMsg
.cont movem.l (sp)+,a6
rts
;Since the user have removed the card we have to queue read-requests
;to that the program calling us won't hang in a loop trying to post an
;io-request to us all the time resulting in that it will hang.
.nocardreadreq move.l IO_UNIT(a1),a0
lea PCM_READLIST(a0),a0
GET SysBase
CALL AddTail
bra.b .cont
cnop 0,4
.cmdtable dc.l 0 ;0 CMD_INVALID
dc.l cmd_reset ;1 CMD_RESET
dc.l cmd_read ;2 CMD_READ
dc.l cmd_write ;3 CMD_WRITE
dc.l 0 ;4 CMD_UPDATE
dc.l cmd_clear ;5 CMD_CLEAR
dc.l 0 ;6 *CMD_STOP
dc.l 0 ;7 *CMD_START
dc.l cmd_flush ;8 CMD_FLUSH
dc.l cmd_query ;9 SDCMD_QUERY
dc.l 0;cmd_break ;a *SDCMD_BREAK
dc.l cmd_setparams ;b SDCMD_SETPARAMS
;========================================================================
;---abortio---
;a6=devicebase
;a1=iorequest
;========================================================================
abortio movem.l a2/a6,-(sp)
GET SysBase
CALL Disable
move.l IO_UNIT(a1),a2
lea PCM_READLIST(a2),a0
move.l a1,-(sp)
bsr.b removeioreq ;queued readreq?
move.l (sp)+,a1
cmp.l PCM_READREQ(a2),a1 ;current readreq?
bne.b .notreadcurr
clr.l PCM_READREMAIN(a2)
bsr.w readdata
bra.b .endabortio
.notreadcurr lea PCM_WRITELIST(a2),a0
move.l a1,-(sp)
bsr.b removeioreq ;queued writereq?
move.l (sp)+,a1
move.l PCM_WRITEREQ(a2),d0
cmp.l d0,a1 ;current writereq?
bne.b .notwritecurr
clr.l PCM_WRITEREMAIN(a2)
move.b #IOERR_ABORTED,IO_ERROR(a1)
bsr.w senddata
.notwritecurr
.endabortio CALL Enable
movem.l (sp)+,a2/a6
rts
;========================================================================
removeioreq ;removes IO-request (a1) if in list (a0).
move.l a0,-(sp)
bsr.b nodeinlist
move.l (sp)+,a0
tst.l d0
beq.b .exit
move.l a1,-(sp)
GET SysBase
CALL Remove
move.l (sp)+,a1
move.b #IOERR_ABORTED,IO_ERROR(a1)
clr.b IO_FLAGS(a1)
CALL ReplyMsg
.exit rts
nodeinlist ;d0 BOOL=nodeinlist(a0 list, a1 node)
move.l LN_SUCC(a0),a0
cmp.l a1,a0
beq.b .found
tst.l (a0)
bne.b nodeinlist
moveq #0,d0
rts
.found move.l a0,d0
rts
;========================================================================
resvec moveq #0,d0
rts
;========================================================================
;---setupdevice--- executed on load of device
;========================================================================
setupdevice move.l a2,-(sp)
moveq #UNITS-1,d0
lea serdata,a2
.initloop lea PCM_RECBUFF(a2),a1 ;init sernode-data
move.l a1,PCM_RECBUFFPTR(a2)
move.l a1,PCM_RECBUFFINPTR(a2)
move.l a1,PCM_RECBUFFOUTPTR(a2)
move.l #10240,PCM_RECBUFFSIZE(a2)
move.l #0,PCM_RECBUFFCURRSIZE(a2)
move.b #0,PCM_FLAGS(a2)
lea PCM_WRITELIST(a2),a1
NEWLIST a1
lea PCM_READLIST(a2),a1
NEWLIST a1
lea PCMNODE_SIZEOF(a2),a2
dbf d0,.initloop
bsr.b initcard
tst.l d0
bne.b .error
bsr.b configurecard
tst.l d0
bne.b .error
moveq #0,d0
bra.b .end
.error moveq #-1,d0
.end move.l (sp)+,a2
rts
;========================================================================
;---cleanupdevice--- executed on expunge
;========================================================================
cleanupdevice bsr.w releasecard
rts
;========================================================================
;---initcard--- Gains ownership of the card.
;========================================================================
initcard: move.l a6,-(sp)
lea cardname(pc),a1
GET SysBase
CALL OpenResource
move.l d0,_CardBase
beq.b .error
GET CardBase
lea cardhandle,a1
CALL OwnCard
tst.l d0
bne.b .error
move.l devicebase(pc),a0
bset #DEVINFOB_OWNCARD,MD_MYFLAGS(a0) ;We own card
lea cardhandle,a1
move.l #CARD_DISABLEF_WP!CARD_ENABLEF_DIGAUDIO,d1
CALL CardMiscControl
moveq #0,d0
bra.b .end
.error moveq #1,d0
.end move.l (sp)+,a6
rts
;========================================================================
;---configurecard--- Confgures the card to show its IO-registers
;========================================================================
configurecard movem.l d2/a6,-(sp)
move.l #CISTPL_FUNCID,d1 ;get functid-tuple
bsr.w .gettuple
tst.l d0
beq.w .error
lea tuplebuffer,a0
cmp.b #2,2(a0) ;is this a modem-card?
bne.w .error
move.l #CISTPL_CFTABLE_ENTRY,d1 ;get confval
bsr.w .gettuple
tst.l d0
beq.w .error
lea tuplebuffer,a0
move.b 2(a0),d0
and.b #$3f,d0 ;this value should be
move.b d0,.confval ;written into CCR
move.l #CISTPL_CONFIG,d1
bsr.w .gettuple
tst.l d0
beq.w .error
lea tuplebuffer,a0
clr.l d2 ;find out the offset
move.b 5(a0),d2 ;to the CCR
lsl.w #8,d2
move.b 4(a0),d2
GET CardBase
CALL GetCardMap
move.l d0,a0
beq.b .error
move.l cmm_AttributeMemory(a0),a1 ;get attribmem base
add.l d2,a1 ;now we have address
move.l a1,confbase ;of the CCR-register
move.b .confval(pc),d0
or.b #$40,d0
move.b d0,(a1) ;Configure card!
or.b #8,2(a1) ;enable audio
move.l cmm_IOMemory(a0),d0
add.l #$10000-$4000,d0
bsr.b .findiobase
move.l d0,iobase
beq.b .error
move.l #CISTPL_FUNCE,d1 ;check if this is
bsr.b .gettuple ;16550 UART with FIFO
lea serdata,a0 ;set up iobase(s)
move.l iobase(pc),PCM_BASEADR(a0)
bclr #STATUSB_USEFIFO,PCM_FLAGS(a0)
tst.l d0
beq.b .fifo
;Found one modem without FUNCE-tuple (Angia 28.8)
;If this is the case we assume 16550-UART
lea tuplebuffer,a1
cmp.b #2,3(a1)
bne.b .nofifo
.fifo bset #STATUSB_USEFIFO,PCM_FLAGS(a0)
.nofifo move.l devicebase(pc),a0
bset #DEVINFOB_CONFIGURED,MD_MYFLAGS(a0) ;Card configged
moveq #0,d0
bra.b .end
.error moveq #-1,d0
.end movem.l (sp)+,d2/a6
rts
.gettuple move.l a6,-(sp)
lea cardhandle(pc),a1
lea tuplebuffer,a0
move.l #100,d0
GET CardBase
CALL CopyTuple
move.l (sp)+,a6
rts
.findiobase move.l d7,-(sp)
move.l d0,a0
lea .iobases(pc),a1
move.w #3,d7
.findbaseloop clr.l d0
move.w (a1)+,d0
move.b #0,UART_MCR(a0,d0)
move.b $bfe001,d1 ;wait a little
btst #1,UART_MCR(a0,d0)
bne.b .nobase
move.b #2,UART_MCR(a0,d0)
move.b $bfe001,d1
btst #1,UART_MCR(a0,d0)
beq.b .nobase
add.l a0,d0 ;iobase found!
bra.b .endfindiobase
.nobase dbf d7,.findbaseloop
clr.l d0 ;iobase not found!
.endfindiobase move.l (sp)+,d7
rts
.iobases dc.w $3f8,$2f8,$3e8,$2e8
.confval dc.b 0
cnop 0,4
;========================================================================
;---releasecard---
;========================================================================
releasecard move.l a6,-(sp)
GET SysBase
CALL Disable
move.l devicebase(pc),a0
btst #DEVINFOB_CONFIGURED,MD_MYFLAGS(a0)
beq.b .notconfigured
move.l confbase(pc),a1
move.b #$80,(a1) ;do a softreset
move.b #0,(a1)
bclr #DEVINFOB_CONFIGURED,MD_MYFLAGS(a0)
.notconfigured btst #DEVINFOB_OWNCARD,MD_MYFLAGS(a0)
beq.b .end
GET CardBase
move.l #CARDF_REMOVEHANDLE,d0
lea cardhandle,a1
CALL ReleaseCard
move.l devicebase(pc),a0
bclr #DEVINFOB_OWNCARD,MD_MYFLAGS(a0)
GET SysBase
CALL Enable
.end move.l (sp)+,a6
rts
_CardBase dc.l 0
cardname: dc.b "card.resource",0
iobase dc.l 0
confbase dc.l 0
cardhandle dc.l 0
dc.l 0
dc.b 0
dc.b 0
dc.l myname
dc.l cardremoveint
dc.l 0
dc.l cardstatusint
dc.b CARDF_IFAVAILABLE
cnop 0,4
cardstatusint dc.l 0
dc.l 0
dc.b 0
dc.b 0
dc.l 0
dc.l 0
dc.l statusintcode
cardremoveint dc.l 0
dc.l 0
dc.b 0
dc.b 0
dc.l 0
dc.l 0
dc.l cardremintcode
;========================================================================
;---cardremintcode--- Shit, that damn user has removed the card!!
;========================================================================
cardremintcode movem.l a2/a6,-(sp)
move.l devicebase(pc),a0 ;mark card as not configured
bclr #DEVINFOB_CONFIGURED,MD_MYFLAGS(a0)
lea serdata,a2
moveq #UNITS-1,d0
.resetloop move.l d0,-(sp)
bsr.w reset ;remove all IO-requests
move.l (sp)+,d0
lea PCMNODE_SIZEOF(a2),a2 ;from all units
dbf d0,.resetloop
movem.l (sp)+,a2/a6
rts
;========================================================================
;---statusintcode---
;========================================================================
statusintcode btst #CARD_STATUSB_IRQ,d0
beq.b .nopcmciairq
movem.l a2/a5/a6,-(sp)
move.w d0,-(sp)
.intloop lea serdata,a2
move.l PCM_BASEADR(a2),a5
move.b UART_IIR(a5),d0
btst #0,d0
bne.b .exit
bra.b .checkint
; bra.b .intloop
.exit move.w (sp)+,d0
move.w d0,d1
eor.b #$2c,d0
or.b #$c0,d0
move.b d0,$da9000 ;nasty workaround for a
;nasty bug i card.resource :(
move.b UART_IIR(a5),d0
btst #0,d0
bne.b .end
move.w #0,d1
move.w d1,-(sp)
bra.b .checkint
.end movem.l (sp)+,a2/a5/a6
move.b #0,d0
.nopcmciairq rts
.checkint and.b #%110,d0
cmp.b #%110,d0
bne.b .nolsrint
bsr.b linestatusint
bra.b .checkintexit
.nolsrint cmp.b #%100,d0
bne.b .norecint
bsr.w recdata
bra.b .checkintexit
.norecint cmp.b #%010,d0
bne.b .notransint
bsr.w senddata
bra.b .checkintexit
.notransint cmp.b #%000,d0
bne.b .nomsrint
bsr.b modemstatusint
.nomsrint
.checkintexit bra.b .intloop
;========================================================================
;---linestatusint--- an error has occured!
;========================================================================
linestatusint: move.b UART_LSR(a5),d0
btst #1,d0 ;Hardware overrun?
beq.b .nooe
move.b #SerErr_LineErr,d0
bra.b .error
.nooe btst #2,d0 ;Parity error?
beq.b .nope
move.b #SerErr_ParityErr,d0
bra.b .error
.nope btst #3,d0 ;Framing error?
beq.b .nofe
move.b #SerErr_LineErr,d0
bra.b .error
.nofe btst #4,d0
beq.b .nobi
move.b #SerErr_DetectedBreak,d0
bra.b .error
.nobi rts
.error tst.l PCM_READREQ(a2) ;is there a current readreq?
beq.b .noreq
move.b #3,UART_FCR(a5) ;clear receive-fifo
move.l PCM_READREQ(a2),a1 ;then abort the shit
clr.l PCM_READREMAIN(a2)
move.b d0,IO_ERROR(a1)
bsr.b readdata
.noreq rts
;========================================================================
;---modemstatusint---
;========================================================================
modemstatusint move.b UART_MSR(a5),d0
btst #4,d0
beq.b .nocts
btst #STATUSB_CTS,PCM_FLAGS(a2) ;CTS activated now?
bne.b .ctscont
bset #STATUSB_CTS,PCM_FLAGS(a2) ;CTS was activated now!
bsr.w senddata ;so resume sending
bra.b .ctscont
.nocts bclr #STATUSB_CTS,PCM_FLAGS(a2) ;stop sending!
.ctscont rts
;========================================================================
;---recdata-- Reads data from UART and buffers it.
;a2=unitptr
;========================================================================
recdata move.l PCM_RECBUFFPTR(a2),a1
move.l PCM_RECBUFFSIZE(a2),d1
add.l d1,a1 ;end_of_buffer ptr
move.l PCM_RECBUFFINPTR(a2),a0 ;current bufferpos
move.l PCM_RECBUFFCURRSIZE(a2),d0 ;current buffersize
.writebuff cmp.l d1,d0 ;recbuffer full?
bne.b .notfull
subq.l #1,d0 ;buff full. Overwrite!
move.l a0,PCM_RECBUFFOUTPTR(a2)
addq.l #1,PCM_RECBUFFOUTPTR(a2)
.notfull move.b UART_RBR(a5),(a0)+ ;read from UART->buffer
addq.l #1,d0
cmp.l a0,a1 ;Will buffer wrap?
bne.b .nowrap
move.l PCM_RECBUFFPTR(a2),a0
.nowrap
btst #0,UART_LSR(a5) ;more data in FIFO?
bne.b .writebuff
move.l a0,PCM_RECBUFFINPTR(a2) ;update bufferpos
move.l d0,PCM_RECBUFFCURRSIZE(a2) ;and size
;no RTS here. Go directly to readdata
;========================================================================
;---readdata-- Reads data from receive-buffer and writes it to IOrequest
;a2=unitptr
;========================================================================
readdata tst.l PCM_READREQ(a2)
beq.b .nodatainbuff
tst.l PCM_READREMAIN(a2)
beq.w .readklar
tst.l PCM_RECBUFFCURRSIZE(a2)
beq.b .nodatainbuff
.moredata move.l PCM_RECBUFFOUTPTR(a2),a0
move.l PCM_READPTR(a2),a1
move.b (a0),d0
move.b d0,(a1)
move.l PCM_READREQ(a2),a1
btst #SERB_EOFMODE,IO_SERFLAGS(a1) ;use EOF-mode?
beq.b .noeofmode
lea IO_TERMARRAY(a1),a0
moveq #7,d1
.checkeofloop cmp.b (a0)+,d0 ;look for termchars
bne.b .noeof
move.l #1,PCM_READREMAIN(a2) ;let's terminate early
.noeof dbf d1,.checkeofloop
.noeofmode addq.l #1,IO_ACTUAL(a1)
addq.l #1,PCM_RECBUFFOUTPTR(a2)
addq.l #1,PCM_READPTR(a2)
subq.l #1,PCM_RECBUFFCURRSIZE(a2)
move.l PCM_RECBUFFOUTPTR(a2),d0
move.l PCM_RECBUFFPTR(a2),d1
add.l PCM_RECBUFFSIZE(a2),d1 ;End of buffer?
cmp.l d0,d1
bne.b .nowrap
move.l PCM_RECBUFFPTR(a2),PCM_RECBUFFOUTPTR(a2)
.nowrap subq.l #1,PCM_READREMAIN(a2)
beq.b .readklar
tst.l PCM_RECBUFFCURRSIZE(a2)
bne.b .moredata
;here the devices internal read-buffer is empty but there is request for
;more bytes, so it's time to activate the receive-FIFO if there is request
;for more than 4 bytes.
.nodatainbuff btst #STATUSB_USEFIFO,PCM_FLAGS(a2)
beq.b .nofifo
move.l PCM_BASEADR(a2),a0
cmp.l #14,PCM_READREMAIN(a2)
bge.b .use14bytes
cmp.l #8,PCM_READREMAIN(a2)
bge.b .use8bytes
cmp.l #4,PCM_READREMAIN(a2)
bge.b .use4bytes
bra.b .use1byte
.use14bytes move.b #%11000001,UART_FCR(a0)
rts
.use8bytes move.b #%10000001,UART_FCR(a0)
rts
.use4bytes move.b #%01000001,UART_FCR(a0)
rts
.use1byte move.b #%00000001,UART_FCR(a0) ;triggerlevel=1 bytes
.nofifo rts
.readklar move.l PCM_READREQ(a2),a1
clr.l PCM_READREQ(a2)
GET SysBase
CALL ReplyMsg
lea PCM_READLIST(a2),a0 ;any queued requests?
CALL RemHead
tst.l d0
beq.w .nodatainbuff
move.l d0,PCM_READREQ(a2) ;activate queued request
move.l d0,a1
move.l IO_DATA(a1),PCM_READPTR(a2)
move.l IO_LENGTH(a1),PCM_READREMAIN(a2)
bra.w readdata
rts
;========================================================================
;---cmd_read---
;a1=IORequest
;========================================================================
cmd_read move.l a2,-(sp)
move.b MD_MYFLAGS(a6),d0 ;we need this one later
clr.b IO_FLAGS(a1) ;no quick IO.
clr.l IO_ACTUAL(a1)
GET SysBase
CALL Disable ;wont trash d0
move.l IO_UNIT(a1),a2
move.l IO_DATA(a1),a0 ;This should not be needed
clr.b (a0) ;but stupid Ncomm requires this
tst.l PCM_READREQ(a2) ;Any pending Requests?
beq.b .noque
.queue
cmp.l PCM_READREQ(a2),a1 ;Stupid NComm strikes again and
beq.b .exit ;tries to send the same IO
;twise without an AbortIO()
lea PCM_READLIST(a2),a0
CALL AddTail
bra.b .exit
.noque move.l a1,PCM_READREQ(a2)
move.l IO_DATA(a1),PCM_READPTR(a2)
move.l IO_LENGTH(a1),PCM_READREMAIN(a2)
bsr.w readdata
.exit CALL Enable
move.l (sp)+,a2
rts
;========================================================================
;---senddata---
;a2=unitptr
;========================================================================
senddata tst.l PCM_WRITEREQ(a2) ;is there really an active
beq.b .nowritereq ;io-request?
tst.l PCM_WRITEREMAIN(a2) ;more bytes to send?
bne.b .sendmore
move.l PCM_WRITEREQ(a2),a1 ;current sendio is ready!
clr.l PCM_WRITEREQ(a2)
clr.l PCM_WRITEREMAIN(a2)
clr.l PCM_WRITEPTR(a2)
move.l a6,-(sp)
GET SysBase
CALL ReplyMsg
lea PCM_WRITELIST(a2),a0
CALL RemHead ;any request in queue
move.l (sp)+,a6
move.l PCM_BASEADR(a2),a0
move.b #%101,UART_FCR(a0) ;clear send-fifo
;(in case of abortio)
tst.l d0
beq.b .noqued
move.l d0,a1 ;activete next request
move.l a1,PCM_WRITEREQ(a2)
move.l IO_DATA(a1),PCM_WRITEPTR(a2)
move.l IO_LENGTH(a1),PCM_WRITEREMAIN(a2)
bra.b .sendmore
.nowritereq
.noqued rts
.sendmore btst #STATUSB_USE7WIRE,PCM_FLAGS(a2) ;CTS/RTS handshake?
beq.b .sendbyte
btst #STATUSB_CTS,PCM_FLAGS(a2) ;Yes
beq.b .nocts
.noctsrts moveq #0,d0
btst #STATUSB_USEFIFO,PCM_FLAGS(a2) ;use send-fifo?
beq.b .sendbyte
moveq #15,d0 ;fill max 16 bytes
.sendbyte move.l PCM_BASEADR(a2),a0
move.l PCM_WRITEPTR(a2),a1
move.b (a1),UART_THR(a0) ;write to UART
addq.l #1,PCM_WRITEPTR(a2)
subq.l #1,PCM_WRITEREMAIN(a2)
beq.b .nocts
move.l PCM_WRITEREQ(a2),a1
addq.l #1,IO_ACTUAL(a1)
dbf d0,.sendbyte
.nocts rts
;========================================================================
;---cmd_write---
;a1=IORequest
;========================================================================
cmd_write move.l a2,-(sp)
clr.b IO_FLAGS(a1)
clr.l IO_ACTUAL(a1)
move.l IO_LENGTH(a1),d0
cmp.l #-1,d0 ;0-terminated?
bne.b .notterm
moveq #0,d0
move.l IO_DATA(a1),a0
.lengthloop tst.b (a0)+
beq.b .notterm
addq.l #1,d0
bra.b .lengthloop
.notterm move.l d0,IO_LENGTH(a1)
GET SysBase
CALL Disable
move.l IO_UNIT(a1),a2
tst.l PCM_WRITEREQ(a2) ;Any pending reuqest?
beq.b .noque
lea PCM_WRITELIST(a2),a0 ;Queue request
CALL AddTail
bra.b .exit
.noque move.l a1,PCM_WRITEREQ(a2)
move.l IO_DATA(a1),PCM_WRITEPTR(a2)
move.l IO_LENGTH(a1),PCM_WRITEREMAIN(a2)
bsr.w senddata
.exit CALL Enable
move.l (sp)+,a2
rts
;========================================================================
;---cmd_query---
;a1=IORequest
;========================================================================
cmd_query move.l a6,-(sp)
move.l IO_UNIT(a1),a0
move.l PCM_BASEADR(a0),a0
move.b UART_MSR(a0),d1
move.w #%00111000,d0
btst #6,d1 ;RING?
beq.b .noring
bset #2,d0
.noring btst #5,d1 ;/DSR?
beq.b .dsr
bclr #3,d0
.dsr btst #4,d1 ;/CTS?
beq.b .cts
bclr #4,d0
.cts btst #7,d1 ;/CD?
beq.b .cd
bclr #5,d0
.cd GET SysBase
CALL Disable
move.l IO_UNIT(a1),a0
move.l PCM_RECBUFFCURRSIZE(a0),IO_ACTUAL(a1)
move.w d0,IO_STATUS(a1)
btst #IOB_QUICK,IO_FLAGS(a1)
bne.b .quickio
CALL ReplyMsg
.quickio CALL Enable
move.l (sp)+,a6
rts
;========================================================================
;---cmd_setparams---
;a1=IORequest
;========================================================================
cmd_setparams move.l a6,-(sp)
GET SysBase
CALL Disable
bsr.b setparams
btst #IOB_QUICK,IO_FLAGS(a1)
bne.b .quickio
CALL ReplyMsg
.quickio CALL Enable
move.l (sp)+,a6
rts
;========================================================================
;---setparams---
;a1=IORequest
;========================================================================
setparams move.l IO_UNIT(a1),a0
move.l PCM_BASEADR(a0),a0
;calc, check and set BAUD
move.l IO_BAUD(a1),d1
cmp.l #115201,d1
bge.w .badbaud
cmp.l #109,d1
bls.w .badbaud
move.l #115200,d0
divu d1,d0
bset #7,UART_LCR(a0) ;set DLAB
move.b d0,UART_DLL(a0)
lsr.w #8,d0
move.b d0,UART_DLM(a0)
bclr #7,UART_LCR(a0) ;clear DLAB
;check and set word length
move.b IO_READLEN(a1),d0
cmp.b IO_WRITELEN(a1),d0
bne.b .badparam
cmp.b #6,IO_READLEN(a1)
bls.b .badparam
cmp.b #9,IO_READLEN(a1)
bge.b .badparam
move.b IO_READLEN(a1),d0
sub.b #5,d0
and.b #$3,d0
and.b #%11111100,UART_LCR(a0)
or.b d0,UART_LCR(a0)
;check and set # of stopbits
cmp.b #1,IO_STOPBITS(a1) ;1 stop bit?
beq.b .1stopbit
cmp.b #2,IO_STOPBITS(a1) ;no, well no more than 2 then?
bne.b .badparam
bset #2,UART_LCR(a0)
bra.b .cont
.1stopbit bclr #2,UART_LCR(a0)
.cont
;check and set parity
and.b #%11000111,UART_LCR(a0) ;mask away parity
btst #SERB_PARTY_ON,IO_SERFLAGS(a1)
beq.b .noparity
bset #3,UART_LCR(a0)
btst #SERB_PARTY_ODD,IO_SERFLAGS(a1)
bne.b .parityodd
bset #4,UART_LCR(a0)
.parityodd
.noparity
rts
.badparam move.b #SerErr_InvParam,IO_ERROR(a1)
rts
.badbaud move.b #SerErr_BaudMismatch,IO_ERROR(a1)
rts
;========================================================================
;---cmd_reset--- removes queued and active IO-requests
;a1=IORequest
;========================================================================
cmd_reset move.l a2,-(sp)
GET SysBase
CALL Disable
move.l IO_UNIT(a1),a2
move.l a1,-(sp)
bsr.b reset
move.l (sp)+,a1
btst #IOB_QUICK,IO_FLAGS(a1)
bne.b .quickio
CALL ReplyMsg
.quickio CALL Enable
move.l (sp)+,a2
rts
;========================================================================
;---reset--- removes queued and active IO-requests
;a2=serunit
;========================================================================
reset bsr.b flush ;remove queued IO-requests
tst.l PCM_READREQ(a2) ;any current read-reqsuests?
beq.b .notreadcurr
clr.l PCM_READREMAIN(a2)
move.l PCM_READREQ(a2),a1
move.b #IOERR_ABORTED,IO_ERROR(a1)
bsr.w readdata
.notreadcurr tst.l PCM_WRITEREQ(a2) ;any current write-requests?
beq.b .exit
clr.l PCM_WRITEREMAIN(a2)
move.l PCM_WRITEREQ(a2),a1
move.b #IOERR_ABORTED,IO_ERROR(a1)
bsr.w senddata
.exit rts
;========================================================================
;---cmd_flush--- flush all queued IO-requests (not active)
;a1=IORequest
;========================================================================
cmd_flush move.l a2,-(sp)
GET SysBase
CALL Disable
move.l IO_UNIT(a1),a2
move.l a1,-(sp)
bsr.b flush
move.l (sp)+,a1
btst #IOB_QUICK,IO_FLAGS(a1)
bne.b .quickio
CALL ReplyMsg
.quickio CALL Enable
move.l (sp)+,a2
rts
;========================================================================
;---flush--- flush all queued IO-requests (not active)
;a2=serunit
;========================================================================
flush lea PCM_READLIST(a2),a0
bsr.b .replylist
lea PCM_WRITELIST(a2),a0
bsr.b .replylist
rts
.replylist move.l a0,-(sp)
CALL RemHead
move.l (sp)+,a0
tst.l d0
bne.b .reply
rts
.reply move.l d0,a1
move.b #IOERR_ABORTED,IO_ERROR(a1)
clr.b IO_FLAGS(a1)
move.l a0,-(sp)
CALL ReplyMsg
move.l (sp)+,a0
bra.b .replylist
;========================================================================
;---cmd_clear--- resets the devices internal readbuffer pointers
;a1=IORequest
;========================================================================
cmd_clear GET SysBase
CALL Disable
move.l IO_UNIT(a1),a0
move.l PCM_RECBUFFPTR(a0),PCM_RECBUFFINPTR(a0)
move.l PCM_RECBUFFPTR(a0),PCM_RECBUFFOUTPTR(a0)
clr.l PCM_RECBUFFCURRSIZE(a0)
btst #IOB_QUICK,IO_FLAGS(a1)
bne.b .quickio
CALL ReplyMsg
.quickio CALL Enable
rts
;========================================================================
;---cmdbreak--- send break (not implemented yet)
;a1=IORequest
;========================================================================
cmd_break GET SysBase
CALL Disable
btst #IOB_QUICK,IO_FLAGS(a1)
bne.b .quickio
CALL ReplyMsg
.quickio CALL Enable
rts
;========================================================================
cnop 0,4
endofcode
section buffers,bss
tuplebuffer ds.b 100
serdata ds.b PCMNODE_SIZEOF*UNITS